home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Language/OS - Multiplatform Resource Library
/
LANGUAGE OS.iso
/
smaltalk
/
manchest.lha
/
MANCHESTER
/
manchester
/
2.3
/
ScrollBars-RHS-NonFlapping.st
< prev
next >
Wrap
Text File
|
1993-07-24
|
18KB
|
624 lines
" NAME Right-sidedNon-flappingScrollBars
AUTHOR Bernard Horan <bernardh@cs.man.ac.uk>
CONTRIBUTOR Bernard Horan <bernardh@cs.man.ac.uk>
FUNCTION persistent scroll bars enclosed in view at RHS
ST-VERSIONS 2.3 & Analyst
PREREQUISITES
CONFLICTS
DISTRIBUTION global
VERSION 1.0
DATE October 1990
SUMMARY A horrible series of hacks to override the existing
implementation of ScrollBars. If the rumours are correct, soon to be
superseded by Smalltalk-80 release 4. [Was it worth it?]. After
filing in the changes, make sure that you close all windows to reset
all the instances of subclasses of ScrollController lying around.
Please report all bugs to me.
"!
'From Smalltalk-80, Version 2.3 of 13 June 1988 on 12 October 1990 at 1:06:51 pm'!
!TextView methodsFor: 'displaying'!
display
"Show the text of the receiver on the display screen."
"Use my clippingBox to determine wrappingBox and the clippingBox (rather than the insetDisplayBox)
BH - 14 March 1990"
self isUnlocked
ifTrue:
[self controller
wrappingBox: (self clippingBox insetBy: 6 @ 0)
clippingBox: self clippingBox.
(controller text isEmpty and: [controller textHasChanged not])
ifTrue: [self newText: self getText]].
super display!
displayView
"Also display the scrollBar and the marker
BH - 14 March 1990"
self topView isCollapsed ifFalse: [
self clearInside.
self controller display ].
self displayScrollBar.
self displayScrollMarker! !
!TextView methodsFor: 'scrolling hacks'!
clippingBox
"return the clippingBox (not including the scrollarea)
BH - 14 March 1990"
^ self insetDisplayBox insetBy: self scrollBarInset!
compositionBox
"Return the compositionBox for the paragraph
BH - 14 March 1990"
^ (self insetDisplayBox insetBy: self paragraphInset) insetBy: self scrollBarInset!
displayScrollBar
"Display the scroll bar
BH - 14 March 1990"
controller scrollBar displayOn: Display!
displayScrollMarker
"display the scrollBar marker
BH - 14 March 1990"
controller marker displayOn: Display.
controller moveMarker!
scrollBarInset
"return the scroll bar inset
BH - 14 March 1990"
^ 0@0 corner: self controller scrollBarWidth@0! !
!DisplayTextView reorganize!
('initialize-release' initialize)
('accessing' centered editParagraph: isCentered mask mask: rule rule:)
('controller access' defaultController defaultControllerClass)
('window access' defaultWindow window:)
('model access' model:)
('displaying' display displayView)
('deEmphasizing' deEmphasizeView)
('private' centerText defaultMask defaultRule paragraphInset positionText)
!
!StringHolderView methodsFor: 'displaying'!
displayView
"also display the scrollBar and the scrollBar marker
BH - 14 March 1990"
self clearInside.
(self controller isKindOf: TextEditor)
ifTrue: [controller display]
ifFalse: [displayContents display].
self displayScrollBar.
self displayScrollMarker!
positionDisplayContents
"Presumably the text being displayed changed so that the wrapping
box and clipping box should be reset."
"Use my clippingBox rather than my insetDisplayBox to get the area
in which the displayCOntents should be displayed
BH - 14 March 1990"
| displayBox translation |
displayBox _ self clippingBox.
displayBox extent = displayContents clippingRectangle extent
ifTrue:
[translation _ displayBox origin - displayContents clippingRectangle origin.
displayContents clippingRectangle: displayBox.
displayContents setCompositionRectangle: (displayContents compositionRectangle translateBy: translation)]
ifFalse: [displayContents recomposeIn: (displayBox insetBy: self paragraphInset)
clippingBox: displayBox]! !
!StringHolderView methodsFor: 'model access'!
editString: aString
"The paragraph to be displayed is created from the characters in
aString. "
"Use my clippingBox to get the clippingBox of the displayContents,
and use my compositionBox to determine its compositionBox, rather
than the insetDisplayBox, since I need to take into account the area
of the scrollBar
BH - 13 March 1990"
displayContents _ TextCompositor
withText: aString asText
style: TextStyle default copy
compositionRectangle: self compositionBox
clippingRectangle: self clippingBox.
(self controller isKindOf: TextEditor)
ifTrue: [controller changeCompositor: displayContents]! !
!StringHolderView methodsFor: 'private'!
paragraphInset
"Answer the amount to inset the paragraph from the border"
^6@0! !
!StringHolderView methodsFor: 'scrolling hacks'!
clippingBox
"return the clippingBox of the view
BH - 14 March 1990"
^ self insetDisplayBox insetBy: self scrollBarInset!
compositionBox
"return the compostionBox of the view
BH - 14 March 1990"
^ (self insetDisplayBox insetBy: self paragraphInset) insetBy: self scrollBarInset!
displayScrollBar
"display the scrollbar
BH - 14 March 1990"
controller scrollBar displayOn: Display!
displayScrollMarker
"display the scrollBar marker
BH - 14 March 1990"
controller marker displayOn: Display.
controller moveMarker!
scrollBarInset
"return the inset for the scroll bar"
^ 0@0 corner: self controller scrollBarWidth@0! !
MouseMenuController subclass: #ScrollController
instanceVariableNames: 'scrollBar marker '
classVariableNames: 'HaltedScrollBar SavedArea ScrollBarWidth '
poolDictionaries: ''
category: 'Interface-Support'!
!ScrollController methodsFor: 'initialize-release'!
initialize
super initialize.
scrollBar _ Quadrangle new.
scrollBar borderWidthLeft: 1 right: 0 top: 2 bottom: 2.
marker _ Quadrangle new.
marker insideColor: Form gray! !
!ScrollController methodsFor: 'basic control sequence'!
controlInitialize
"Don't do anything more than my super
BH - 14 March 1990"
super controlInitialize!
controlTerminate
"Don't do anything more than my super.
BH - 14 March 1990"
super controlTerminate!
newcontrolInitialize
"The scrollbar has a two-pixel border, and for alignment it assumes that this sub-view
has a one-pixel border and shares another one-pixel border from its neighbor/super view"
"super controlInitialize.Z"
self scrollBar.
self marker.
"scrollBar region: (0@0 extent: 15 @ (view displayBox height + 2)).
marker region: self computeMarkerRegion.
scrollBar _ scrollBar align: scrollBar topRight with: view displayBox topRight + (0@ -1).
marker _ marker align: marker topCenter with: scrollBar inside topCenter.
self class getSavedAreaFor: scrollBar.
scrollBar displayOn: Display.
self moveMarker"!
oldcontrolInitialize
"The scrollbar has a two-pixel border, and for alignment it assumes that this sub-view
has a one-pixel border and shares another one-pixel border from its neighbor/super view"
"super controlInitialize.Z"
scrollBar region: (0@0 extent: 15 @ (view displayBox height + 2)).
marker region: self computeMarkerRegion.
scrollBar _ scrollBar align: scrollBar topRight with: view displayBox topRight + (0@ -1).
marker _ marker align: marker topCenter with: scrollBar inside topCenter.
self class getSavedAreaFor: scrollBar.
scrollBar displayOn: Display.
self moveMarker! !
!ScrollController methodsFor: 'scrolling'!
newscroll
"Only absolute scrolling now allowed - BH - 5 September 1989"
| savedCursor regionPercent |
savedCursor _ sensor currentCursor.
[self scrollBarContainsCursor]
whileTrue:
[Processor yield.
self changeCursor: Cursor marker.
(Sensor anyButtonPressed) ifTrue:[self scrollAbsolute]].
savedCursor show!
oldscroll
"Check to see whether the user wishes to jump, scroll up, or scroll down."
| savedCursor regionPercent |
savedCursor _ sensor currentCursor.
[self scrollBarContainsCursor]
whileTrue:
[Processor yield.
regionPercent _ 100 * (sensor cursorPoint x - scrollBar left) // scrollBar width.
regionPercent <= 40
ifTrue: [self scrollDown]
ifFalse: [regionPercent >= 60
ifTrue: [self scrollUp]
ifFalse: [self scrollAbsolute]]].
savedCursor show!
oldscrollAmount
"Answer the number of bits of y-coordinate should be scrolled. This is a
default determination based on the view's preset display transformation."
^((view inverseDisplayTransform: sensor cursorPoint)
- (view inverseDisplayTransform: scrollBar inside topCenter)) y!
scroll
"Check to see whether the user wishes to jump, scroll up, or scroll
down."
"BH - 12 October 1990"
| savedCursor |
savedCursor _ sensor currentCursor.
[self scrollBarContainsCursor]
whileTrue:
[Processor yield.
self changeCursor: Cursor scroll.
Sensor anyButtonPressed ifTrue: [sensor cursorPoint y < marker top
ifTrue:
[self scrollDown.
[Sensor anyButtonPressed]
whileTrue:
[self scrollView: 1.
self moveMarker]]
ifFalse: [sensor cursorPoint y > marker bottom
ifTrue:
[self scrollUp.
[Sensor anyButtonPressed]
whileTrue:
[self scrollView: -1.
self moveMarker]]
ifFalse: [self scrollAbsolute]]]].
savedCursor show!
scrollAmount
^(sensor cursorPoint - marker center) y abs! !
!ScrollController methodsFor: 'marker adjustment'!
computeMarkerRegion
"Answer the rectangular area in which the gray area of the scroll bar
should be displayed."
"BH - 15 March 1990"
^0@0 extent: (self scrollBarWidth - 5) @
((view window height asFloat /
view boundingBox height *
scrollBar inside height)
rounded min: scrollBar inside height)! !
!ScrollController methodsFor: 'private'!
scrollAbsolute
"Different cursor"
"BH - 12 October 1990"
| oldMarker |
self changeCursor: Cursor upDown.
self canScroll & sensor anyButtonPressed ifTrue:
[[sensor anyButtonPressed] whileTrue:
[oldMarker _ marker.
marker _ marker translateBy:
0@((sensor cursorPoint y - marker center y min:
scrollBar inside bottom - marker bottom) max: scrollBar inside top - marker top).
(oldMarker areasOutside: marker), (marker areasOutside: oldMarker) do:
[:region | Display fill: region rule: Form reverse mask: Form gray].
self scrollView].
scrollBar display.
self moveMarker]!
scrollDown
"Different cursor, continuous scrolling"
"BH - 12 October 1990"
self canScroll
ifTrue:
[self changeCursor: Cursor up.
self scrollViewDown.
self moveMarker]!
scrollUp
"Different cursor, continuous scrolling"
"BH - 12 October 1990"
self canScroll
ifTrue:
[self changeCursor: Cursor down.
self scrollViewUp.
self moveMarker]! !
!ScrollController methodsFor: 'scrolling hacks'!
marker
"BH - 14 March 1990"
marker region: self computeMarkerRegion.
^ marker _ marker align: marker topCenter with: scrollBar inside topCenter!
scrollBar
"BH - 14 March 1990"
scrollBar region: (0@0 extent: self scrollBarWidth @ (view displayBox height + 2)).
^ scrollBar _ scrollBar align: scrollBar topRight with: view displayBox topRight + (0@ -1)!
scrollBarWidth
"BH - 14 March 1990"
^ self class scrollBarWidth! !
!ListController methodsFor: 'scrolling'!
oldscrollAmount
^sensor cursorPoint y - scrollBar inside top!
scrollAmount
^super scrollAmount! !
!Cursor class methodsFor: 'constants'!
scroll
"Answer the instance of the receiver that is up and down arrows."
^ (self classVarNames includes: #UpDownCursor)
ifTrue:[UpDownCursor]
ifFalse:[ScrollCursor]!
upDown
^ self scroll! !
!FillInTheBlankView methodsFor: 'scrolling hack'!
displayView
"do not diaply scroll bar or marker"
"BH - 12 October 1990"
self clearInside.
(self controller isKindOf: TextEditor)
ifTrue:[controller display]
ifFalse:[displayContents display]! !
!FillInTheBlankView class methodsFor: 'instance creation'!
on: aFillInTheBlank message: messageString displayAt: originPoint centered: centered useCRController: useCRController
| topView messageView answerView |
messageView _ self buildMessageView: messageString.
answerView _
self buildAnswerView: aFillInTheBlank
frameWidth: messageView window width.
useCRController ifTrue: [answerView controller: CRFillInTheBlankController new].
topView _ View new model: aFillInTheBlank.
topView controller: BinaryChoiceController new.
topView addSubView: messageView.
topView addSubView: answerView below: messageView.
topView align: (centered
ifTrue: [topView viewport center]
ifFalse: [topView viewport topLeft])
with: originPoint.
topView window:
(0 @ 0 extent:
messageView window width @
(messageView window height + answerView window height)).
topView translateBy:
(topView displayBox amountToTranslateWithin: Display boundingBox).
^topView! !
!ListView reorganize!
('initialize-release' initialize)
('list access' list list: reset resetAndDisplayView)
('delimiters' bottomDelimiter bottomDelimiter: noBottomDelimiter noTopDelimiter topDelimiter topDelimiter:)
('displaying' display displaySelectionBox displayView)
('deEmphasizing' deEmphasizeView emphasizeView)
('controller access' defaultControllerClass)
('display box access' boundingBox)
('clipping box access' clippingBox)
('selecting' deselect findSelection: isSelectionBoxClipped maximumSelection minimumSelection moveSelectionBox: selection selectionBox selectionBoxOffset)
('updating' update:)
('private' computeCompositionOrigin positionList wrappingBox)
('scrolling hacks' displayScrollBar displayScrollMarker scrollBarInset)
!
!ListView methodsFor: 'displaying'!
displayView
"Also display the scrollBar and the scrollBar marker
BH - 14 March 1990"
self clearInside.
list displayOn: Display.
self displaySelectionBox.
self displayScrollBar.
self displayScrollMarker! !
!ListView methodsFor: 'clipping box access'!
clippingBox
"Answer the rectangle in which the model can be displayed--this
is the insetDisplayBox inset by the height of a line for an item."
"also inset by the scrollBar inset
BH - 14 March 1990"
^(self insetDisplayBox insetBy:
(Rectangle
left: 0
right: 0
top: 0
bottom: self insetDisplayBox height \\ list lineGrid)) insetBy: self scrollBarInset! !
!ListView methodsFor: 'scrolling hacks'!
displayScrollBar
"display the scroll bar
BH - 14 March 1990"
controller scrollBar displayOn: Display!
displayScrollMarker
"display the scrollBar marker
BH - 14 March 1990"
controller marker displayOn: Display.
controller moveMarker!
scrollBarInset
"return the scroll bar inset
BH - 14 March 1990"
^ 0@0 corner: self controller scrollBarWidth@0! !
!ScrollController class methodsFor: 'class initialization'!
initialize
"ScrollController initialize"
"BH - 14 March 1990"
ScrollBarWidth _ 15! !
!ScrollController class methodsFor: 'scrolling hacks'!
scrollBarWidth
"BH - 14 March 1990"
^ ScrollBarWidth! !
ScrollController initialize!
!ParagraphEditor methodsFor: 'scrolling'!
oldscrollAmount
^sensor cursorPoint y - scrollBar top!
scrollAmount
^super scrollAmount! !
!ParagraphEditor methodsFor: 'menu messages'!
cancel
"Restore the text of the paragraph to be the text saved since initialization or
the last accept."
self controlTerminate.
UndoSelection _ paragraph text.
view clearInside.
view displayScrollBar.
view displayScrollMarker.
self changeParagraph: (paragraph text: initialText).
paragraph displayOn: Display.
self scrollToTop.
self controlInitialize! !
!Controller reorganize!
('initialize-release' initialize release)
('model access' model model:)
('view access' view view:)
('sensor access' sensor sensor:)
('basic control sequence' controlInitialize controlLoop controlTerminate startUp)
('control defaults' controlActivity controlToNextLevel isControlActive isControlWanted)
('cursor' centerCursorInView viewHasCursor)
('scrolling hacks' marker moveMarker scrollBar scrollBarWidth)
!
!Controller methodsFor: 'scrolling hacks'!
marker
^ Form extent: 0@0!
moveMarker
^ self!
scrollBar
^ Form extent: 0@0!
scrollBarWidth
^ 0! !
!TextEditor methodsFor: 'scrolling'!
oldscrollAmount
| lineLength |
lineLength _ paragraph lineLength.
lineLength <= 1 ifTrue: [^lineLength].
^lineLength - 1 min: (((super scrollAmount) asFloat
/ paragraph lineGrid asFloat) truncated max: 1)!
scrollAbsolute
"New cursor"
"BH - 12 October 1990"
| oldMarker delta newMarkerRegion oldCursorY cursorY offsetY |
self changeCursor: Cursor scroll.
oldCursorY _ marker center y.
self canScroll & sensor anyButtonPressed ifTrue:
[[sensor anyButtonPressed] whileTrue:
[oldMarker _ marker copy.
cursorY _ sensor cursorPoint y.
delta _ ((marker center y - cursorY) asFloat / scrollBar inside height asFloat
* (paragraph textSize max: 1) asFloat) truncated.
(oldCursorY - cursorY) * delta <= 0 ifTrue: [delta _ 0].
self scrollView: delta.
oldCursorY _ cursorY.
newMarkerRegion _ self computeMarkerRegion.
offsetY _ (((paragraph lines at: 1) - 1) asFloat
/ (paragraph textSize max: 1) asFloat
* scrollBar inside height asFloat) rounded
min: scrollBar inside height - newMarkerRegion height.
marker region: (marker left@(scrollBar inside top + offsetY) extent: newMarkerRegion corner).
(oldMarker areasOutside: marker), (marker areasOutside: oldMarker) do:
[:region | Display fill: region rule: Form reverse mask: Form gray]].
scrollBar display.
self moveMarker]!
scrollDown
"Different cursor, continuous scrolling"
"BH - 12 October 1990"
self canScroll
ifTrue:
[self changeCursor: Cursor up.
self scrollViewDown.
self moveMarker]!
scrollUp
"Different cursor, continuous scrolling"
"BH - 12 October 1990"
self canScroll
ifTrue:
[self changeCursor: Cursor down.
self scrollViewUp.
self moveMarker]! !
!TextEditor methodsFor: 'menu messages'!
cancel
"Restore the text of the paragraph to be the text saved since initialization or
the last accept."
self controlTerminate.
UndoSelection _ paragraph text.
view clearInside.
view displayScrollBar.
view displayScrollMarker.
paragraph resetState.
self changeCompositor: (paragraph text: initialText).
paragraph displayOn: Display.
self scrollToTop.
self controlInitialize! !